Initialize Plants module
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
character(len=300), | intent(in) | :: | iniFile |
configuration file |
||
type(grid_integer), | intent(in) | :: | mask |
mask of simulation domain |
||
type(DateTime), | intent(in) | :: | begin |
simulation starting date |
||
type(DateTime), | intent(in) | :: | end |
simulation ending date |
Type | Visibility | Attributes | Name | Initial | |||
---|---|---|---|---|---|---|---|
character(len=300), | public | :: | ICfile | ||||
character(len=300), | public | :: | PMfile | ||||
integer(kind=short), | public | :: | i | ||||
type(IniList), | public | :: | iniDB |
store configuration info |
|||
integer(kind=short), | public | :: | j | ||||
integer(kind=short), | public | :: | k | ||||
real(kind=float), | public | :: | scalar | ||||
character(len=300), | public | :: | species_file |
SUBROUTINE PlantsConfig & ! (iniFile, mask, begin, end) IMPLICIT NONE ! Arguments with intent(in): CHARACTER (LEN = 300), INTENT(IN) :: iniFile !!configuration file TYPE (grid_integer), INTENT(IN) :: mask !!mask of simulation domain TYPE (DateTime), INTENT (IN) :: begin !!simulation starting date TYPE (DateTime), INTENT(IN) :: end !!simulation ending date !local declarations: TYPE(IniList) :: iniDB !!store configuration info INTEGER (KIND = short) :: i, j, k CHARACTER (LEN = 300) :: species_file CHARACTER (LEN = 300) :: ICfile CHARACTER (LEN = 300) :: PMfile REAL (KIND = float) :: scalar !------------end of declaration------------------------------------------------ CALL IniOpen (iniFile, iniDB) !need plants dynamic simulation? simulatePlants = IniReadInt ('plants-simulation', iniDB) IF ( simulatePlants == 1) THEN !plants dynamic is simulated: configure forest model !plants mask IF ( SectionIsPresent ( 'plants-mask', iniDB) ) THEN CALL GridByIni (iniDB, plants_mask, section = 'plants-mask') ELSE CALL Catch ('error', 'Plants', 'Mask missing in configuration file') END IF !CO2 modifier IF ( SectionIsPresent ( 'use-co2-modifier', iniDB) ) THEN IF ( IniReadInt ('use-co2-modifier', iniDB) == 1 ) THEN useCO2modifier = .TRUE. ELSE useCO2modifier = .FALSE. END IF ELSE !if key is not found, set it to default false useCO2modifier = .FALSE. END IF !mortality IF ( KeyIsPresent ( 'mortality', iniDB) ) THEN IF ( IniReadInt ('mortality', iniDB) == 1 ) THEN mortality = .TRUE. ELSE mortality = .FALSE. END IF ELSE !if mortality is not found, assume it is not considered mortality = .FALSE. END IF !load species species_file = IniReadString ('plants-species-file', iniDB) CALL ReadSpecies (species_file) !compute number of stands and allocate count_stands = 0 DO i = 1, plants_mask % idim DO j = 1, plants_mask % jdim IF ( plants_mask % mat (i,j) /= plants_mask % nodata ) THEN count_stands = count_stands + 1 END IF END DO END DO ALLOCATE ( forest ( count_stands) ) !initialize list k = 1 DO i = 1, plants_mask % idim DO j = 1, plants_mask % jdim IF ( plants_mask % mat (i,j) /= plants_mask % nodata ) THEN !initialize the first cohort in the stand ALLOCATE ( forest (k) % first) NULLIFY ( forest (k) % first % next) forest (k) % lenght = 1 !store position of stand forest (k) % i = i forest (k) % j = j k = k + 1 END IF END DO END DO !set initial condition ICfile = IniReadString ('plants-ic-file', iniDB) CALL SetIC (ICfile) !set plants management options IF (KeyIsPresent ('plants-management-file',iniDB) ) THEN plants_management = .TRUE. PMfile = IniReadString ('plants-management-file', iniDB) CALL SetPlantsManagement (PMfile, begin, end) !set management pratice for each stand DO k = 1, count_stands CALL SetPractice ( management_map % mat (forest (k) % i, forest (k) % j) , forest (k) % thinning ) END DO ELSE !management is turned off plants_management = .FALSE. END IF !set interception maps if required IF (interceptionParametersByMap == 0 ) THEN CALL Catch ('warning', 'Plants', 'interception parameters are set only where plants map is not nodata') !allocate maps CALL NewGrid (laimax, plants_mask) CALL NewGrid (canopymax, plants_mask) DO k = 1, count_stands i = forest (k) % i j = forest (k) % j laimax % mat (i,j) = forest (k) % first % species % laimax canopymax % mat (i,j) = forest (k) % first % species % canopymax END DO END IF !allocate grids for state variables CALL NewGrid (lai, plants_mask) CALL NewGrid (fvcover, plants_mask) CALL NewGrid (gpp, plants_mask) CALL NewGrid (npp, plants_mask) CALL NewGrid (carbonroot, plants_mask) CALL NewGrid (carbonstem, plants_mask) CALL NewGrid (carbonleaf, plants_mask) CALL NewGrid (dbh, plants_mask) CALL NewGrid (plantsHeight, plants_mask) CALL NewGrid (density, plants_mask) CALL NewGrid (stemyield, plants_mask) !fill in grids CALL ForestToGrid (lai, 'lai') CALL ForestToGrid (fvcover, 'fv') CALL ForestToGrid (gpp, 'gpp') CALL ForestToGrid (npp, 'npp') CALL ForestToGrid (carbonroot, 'root') CALL ForestToGrid (carbonstem, 'stem') CALL ForestToGrid (carbonleaf, 'leaf') CALL ForestToGrid (dbh, 'dbh') CALL ForestToGrid (plantsHeight, 'height') CALL ForestToGrid (density, 'density') CALL ForestToGrid (stemyield, 'stemyield') fvcoverLoaded = .TRUE. laiLoaded = .TRUE. plantsHeightLoaded = .TRUE. ELSE ! no plants dynamic simulation required: read parameters from files !leaf area index IF ( SectionIsPresent ( 'lai', iniDB) ) THEN IF (KeyIsPresent ('scalar', iniDB, 'lai') ) THEN scalar = IniReadReal ('scalar', iniDB, 'lai') CALL NewGrid (lai, mask, scalar) ELSE !check if parameter may change in time IF (KeyIsPresent ('format', iniDB, 'lai') ) THEN IF ( IniReadString ('format', iniDB, 'lai') == 'net-cdf' ) THEN updatePlantsParameters = .TRUE. END IF END IF !read map CALL GridByIni (iniDB, lai, section = 'lai') END IF laiLoaded = .TRUE. ELSE CALL Catch ('warning', 'Plants', 'LAI missing in configuration file') END IF !fraction of vegetation coverage IF ( SectionIsPresent ( 'vegetation-fraction', iniDB) ) THEN IF (KeyIsPresent ('scalar', iniDB, 'vegetation-fraction') ) THEN scalar = IniReadReal ('scalar', iniDB, 'vegetation-fraction') CALL NewGrid (fvcover, mask, scalar) ELSE !check if parameter may change in time IF (KeyIsPresent ('format', iniDB, 'vegetation-fraction') ) THEN IF ( IniReadString ('format', iniDB, 'vegetation-fraction') == 'net-cdf' ) THEN updatePlantsParameters = .TRUE. END IF END IF !read map CALL GridByIni (iniDB, fvcover, section = 'vegetation-fraction') END IF fvcoverLoaded = .TRUE. ELSE CALL Catch ('warning', 'Plants', 'vegetation-fraction is missing') END IF !plants height IF ( SectionIsPresent ( 'vegetation-height', iniDB) ) THEN IF (KeyIsPresent ('scalar', iniDB, 'vegetation-height') ) THEN scalar = IniReadReal ('scalar', iniDB, 'vegetation-height') CALL NewGrid (plantsHeight, mask, scalar) ELSE !check if parameter may change in time IF (KeyIsPresent ('format', iniDB, 'vegetation-height') ) THEN IF ( IniReadString ('format', iniDB, 'vegetation-height') == 'net-cdf' ) THEN updatePlantsParameters = .TRUE. END IF END IF !read map CALL GridByIni (iniDB, plantsHeight, section = 'vegetation-height') END IF plantsHeightLoaded = .TRUE. ELSE CALL Catch ('warning', 'Plants', 'vegetation-height is missing') END IF END IF !minimum stomatal resistance. this is not computed by forest model and it may be used for computing PET IF ( SectionIsPresent ( 'min-stomatal-resistance', iniDB) ) THEN IF (KeyIsPresent ('scalar', iniDB, 'min-stomatal-resistance') ) THEN scalar = IniReadReal ('scalar', iniDB, 'min-stomatal-resistance') CALL NewGrid (rsMin, mask, scalar) ELSE !check if parameter may change in time IF (KeyIsPresent ('format', iniDB, 'min-stomatal-resistance') ) THEN IF ( IniReadString ('format', iniDB, 'min-stomatal-resistance') == 'net-cdf' ) THEN updatePlantsParameters = .TRUE. END IF END IF !read map CALL GridByIni (iniDB, rsMin, section = 'min-stomatal-resistance') END IF rsMinLoaded = .TRUE. ELSE CALL Catch ('warning', 'Plants', 'min-stomatal-resistance is missing') END IF CALL IniClose (iniDB) RETURN END SUBROUTINE PlantsConfig